home *** CD-ROM | disk | FTP | other *** search
-
- /* Copyright (C) 1988, 1989 Herve' Touati, Aquarius Project, UC Berkeley */
-
- /* Copyright Herve' Touati, Aquarius Project, UC Berkeley */
-
- #include <stream.h>
- #include "tags.h"
- #include "instr.h"
- #include "hash_table.h"
- #include "string_table.h"
- #include "memory.h"
- #include "basics.h"
- #include "top_level.h"
-
- unsigned MODE;
-
- /* conventions: */
- /* a DATA POINTER is stored as an OFFSET from H0 */
- /* a STACK POINTER register is stored by casting it to UNSIGNED */
- /* a CODE POINTER is stored by casting it to UNSIGNED */
-
- Cell Deref(register Cell Ref)
- {
- while (get_tag(Ref) == TAGREF) {
- register Cell Val = lvalue(Ref);
- if (Ref == Val) break;
- Ref = Val;
- }
- return Ref;
- }
-
- unsigned unify(register Cell arg1, register Cell arg2)
- {
- top_of_the_loop:
- arg1 = deref(arg1);
- arg2 = deref(arg2);
- if (get_tag(arg1) == get_tag(arg2)) {
- switch(get_tag(arg1)) {
- case TAGREF:
- if (arg1 > arg2)
- Bind(arg1, arg2);
- else
- Bind(arg2, arg1);
- return UNIFY_SUCCESS;
- case TAGLIST:
- {
- if (arg1 == arg2) return UNIFY_SUCCESS;
- CellPtr S1 = addr(arg1);
- CellPtr S2 = addr(arg2);
- if (! unify(S1[0], S2[0])) return UNIFY_FAIL;
- arg1 = S1[1];
- arg2 = S2[1];
- goto top_of_the_loop;
- }
- case TAGSTRUCT:
- {
- if (arg1 == arg2) return UNIFY_SUCCESS;
- CellPtr S1 = addr(arg1);
- CellPtr S2 = addr(arg2);
- if (S1[0] != S2[0]) return UNIFY_FAIL;
- int i0 = get_int(S1[1]) + 2;
- for (int i = 2; i < i0; i++)
- if (! unify(S1[i], S2[i])) return UNIFY_FAIL;
- break;
- }
- case TAGCONST:
- return (arg1 == arg2) ? UNIFY_SUCCESS : UNIFY_FAIL;
- default:
- top_level_error("strange tag encountered");
- break;
- }
- } else if (get_tag(arg1) == TAGREF) {
- Bind(arg1, arg2);
- return UNIFY_SUCCESS;
- } else if (get_tag(arg2) == TAGREF) {
- Bind(arg2, arg1);
- return UNIFY_SUCCESS;
- } else {
- return UNIFY_FAIL;
- }
- }
-
- /* Special halt instruction */
- void Halt()
- {
- cout << "\t\t\t*** HALT *** \n";
- top_level_normal_termination();
- }
-
- void Fail()
- {
- /* undo the trailed bindings */
- /* the trail stack grows downwards */
- /* the trail entries are guaranteed to be unbound variables */
- register Cell* tr = TR + 1;
- register Cell* tr0 = cellp(B[TR_CP_OFFSET]);
- for (; tr <= tr0; tr++)
- lvalue(*tr) = *tr;
- TR = tr0;
-
- /* read the topmost choice point back into registers */
- E = cellp(B[E_CP_OFFSET]);
- H = cellp(B[H_CP_OFFSET]);
- TR = cellp(B[TR_CP_OFFSET]);
- P = instrp(B[P_CP_OFFSET]);
- int i0 = B[SIZE_CP_OFFSET];
- for (int i = 0; i < i0; i++)
- X[i] = B[X1_CP_OFFSET + i];
-
- #ifdef WITH_GC
- if (H < HMIN) {
- H2 = H;
- TR2 = TR;
- E2 = E;
- H = HMIN;
- }
- #endif
- }
-
-